perm filename DTSPEC.MSS[WHT,LSP] blob
sn#754057 filedate 1984-05-12 generic text, type T, neo UTF8
@Part[Dtspec, Root = "CLM.MSS"]
@Comment{Chapter of Common Lisp Manual. Copyright 1984 Guy L. Steele Jr.⎇
@MyChapter[Type Specifiers]
@Label[DTSPEC]
In @clisp, types are named by @xlisp objects, specifically symbols and lists,
called @Def[type specifiers]. Symbols name predefined classes of objects,
whereas lists usually indicate combinations or
specializations of simpler types.
Symbols or lists may also be abbreviations for types that could
be specified in other ways.
@Section[Type Specifier Symbols]
The type symbols defined by the system include those shown in Table
@Ref[TYPE-SYMBOLS-TABLE].
In addition, when a structure type is defined using @Macref[defstruct],
the name of the structure type becomes a valid type symbol.
@Section[Type Specifier Lists]
If a type specifier is a list, the @i[car]
of the list is a symbol, and the rest of the list is subsidiary
type information. In many cases a subsidiary item may be
@i[unspecified]. The unspecified subsidiary item is indicated
by writing @f[*]. For example, to completely specify
a vector type, one must mention the type of the elements
and the length of the vector, as for example
@lisp
(vector double-float 100)
@endlisp
To leave the length unspecified, one would write
@lisp
(vector double-float *)
@endlisp
To leave the element type unspecified, one would write
@lisp
(vector * 100)
@endlisp
Suppose that two type specifiers are the same except that the first
has a @f[*] where the second has a more explicit specification.
Then the second denotes a subtype of the type denoted by the first.
As a convenience, if a list
has one or more unspecified items at the end, such items
may simply be dropped rather than writing an explicit @f[*] for each one.
If dropping all occurrences of @f[*] results in a singleton list,
then the parentheses may be dropped as well (the list may be replaced
by the symbol in its @i[car]). For example,
@f[(vector double-float *)] may be abbreviated to @f[(vector double-float)],
and @f[(vector * *)] may be abbreviated to @f[(vector)] and then to
simply @f[vector].
@Section[Predicating Type Specifiers]
A type specifier list @f[(satisfies @i[predicate-name])] denotes
the set of all objects that satisfy the predicate named by @i[predicate-name],
which must be a symbol whose global function definition is a one-argument
predicate.
(A name is required; lambda-expressions are not allowed in order to avoid
scoping problems.) For example, the type @f[(satisfies numberp)] is the
same as the type @f[number].
The call @f[(typep x '(satisfies p))] results in applying @f[p] to @f[x]
and returning @f[t] if the result is true and @nil if the result is false.
As an example, the type @f[string-char] could be defined as
@lisp
(deftype string-char () '(and character (satisfies string-char-p)))
@endlisp
See @Macref[deftype].
It is not a good idea for
a predicate appearing in a @f[satisfies] type specifier to
cause any side effects when invoked.
@Begin[Table]
@Mline[]
@Caption[Standard Type Specifier Symbols]
@Tag[TYPE-SYMBOLS-TABLE]
@Lisp
@Tabdivide[4]
array@\fixnum@\package@\simple-vector
atom@\float@\pathname@\single-float
bignum@\function@\random-state@\standard-char
bit@\hash-table@\ratio@\stream
bit-vector@\integer@\rational@\string
character@\keyword@\readtable@\string-char
common@\list@\sequence@\symbol
compiled-function@\long-float@\short-float@\t
complex@\nil@\simple-array@\vector
cons@\null@\simple-bit-vector
double-float@\number@\simple-string
@Endlisp
@Mline[]
@End[Table]
@Section[Type Specifiers that Combine]
The following type specifier lists define a data type in terms of
other types or objects.
@Begin[Description]
@Begin[Multiple, need 2]
@f[(member @i[object1] @i[object2] ...)]@\This denotes the set
containing precisely those objects named. An object is of
this type if and only if it is @Funref[eql] to one of the specified objects.
@Incompatibility{This is approximately equivalent to what
the @interlisp DECL package calls @f[memq].⎇
@End[Multiple]
@Begin[Multiple, need 2]
@f[(not @i[type])]@\This denotes the set of all those objects that
are @i[not] of the specified type.
@End[Multiple]
@Begin[Multiple, need 2]
@f[(and @i[type1] @i[type2] ...)]@\This denotes the intersection of the specified types.
@Incompatibility{This is roughly equivalent to what
the @interlisp DECL package calls @f[allof].⎇
When @Funref[typep] processes an @f[and] type specifier, it always
tests each of the component types in order from left to right
and stops processing as soon as one component of the intersection has
been found to which the object in question does not belong.
In this respect an @f[and] type specifier is similar to an
executable @Macref[and] form. The purpose of this similarity is to allow
a @f[satisfies] type specifier to depend on filtering by previous
type specifiers. For example, suppose there were a function @f[primep]
that takes an integer and says whether it is prime. Suppose also that
it is an error to give any object other than an integer to @f[primep].
Then the type specifier
@lisp
(and integer (satisfies primep))
@endlisp
is guaranteed never to result in an error because the function @f[primep]
will not be invoked unless the object in question has already been
determined to be an integer.
@End[Multiple]
@Begin[Multiple, need 2]
@f[(or @i[type1] @i[type2] ...)]@\This denotes the union of the specified
types. For example, the type @f[list] by definition is the same as
@f[(or null cons)]. Also, the value returned by the function
@Funref[position] is always of type @f[(or null (integer 0 *))]
(either @nil or a non-negative integer).
@Incompatibility{This is roughly equivalent to what
the @interlisp DECL package calls @f[oneof].⎇
As for @f[and],
when @f[typep] processes an @f[or] type specifier, it always
tests each of the component types in order from left to right
and stops processing as soon as one component of the union has
been found to which the object in question belongs.
@End[Multiple]
@End[Description]
@Section[Type Specifiers that Specialize]
Some type specifier lists denote @i[specializations] of
data types named by symbols. These specializations may be
reflected by more efficient representations in the underlying
implementation. As an example, consider the type @f[(array short-float)].
Implementation A may choose to provide a specialized representation
for arrays of short floating-point numbers, and implementation B
may choose not to.
If you should want to create an array for the
express purpose of holding only short-float objects, you may
optionally specify to @Funref[make-array] the element type
@f[short-float]. This does not @i[require] @f[make-array] to create
an object of type @f[(array short-float)]; it merely @i[permits] it. The
request is construed to mean, ``Produce the most specialized array
representation capable of holding short-floats that the implementation
can provide.'' Implementation A will then produce a specialized
array of type @f[(array short-float)], and implementation B
will produce an ordinary array of type @f[(array t)].
If one were then to ask whether the array were actually of type
@f[(array short-float)], implementation A would say ``yes,'' but
implementation B would say ``no.'' This is a property of @f[make-array]
and similar functions: what you ask for is not necessarily what you get.
Types can therefore be used for two different purposes:
@i[declaration] and @i[discrimination]. Declaring to @f[make-array]
that elements will always be of type @f[short-float] permits
optimization. Similarly, declaring that a variable takes on
values of type @f[(array short-float)] amounts to saying that
the variable will take on values that might be produced by specifying
element type @f[short-float] to @f[make-array].
On the other hand, if the predicate @f[typep] is used to test
whether an object is of type @f[(array short-float)],
only objects actually of that specialized type can satisfy the test;
in implementation B no object can pass that test.
The valid list-format names for data types are as follows:
@Begin[Description]
@Begin[Multiple, need 2]
@f[(array @i[element-type] @i[dimensions])]@\This denotes the set
of specialized arrays
whose elements are all members of the type @i[element-type]
and whose dimensions match @i[dimensions].
For declaration purposes, this type encompasses those arrays
that can result by specifying @i[element-type] as the element type
to the function @Funref[make-array]; this may be different
from what the type means for discrimination purposes.
@i[element-type] must be a valid type specifier or unspecified.
@i[dimensions] may be a non-negative integer, which is the number
of dimensions, or it may be a list of non-negative integers
representing the length of each dimension (any dimension
may be unspecified instead), or it may be unspecified.
For example:
@lisp
(array integer 3) ;@r[Three-dimensional arrays of integers]
(array integer (* * *)) ;@r[Three-dimensional arrays of integers]
(array * (4 5 6)) ;@r[4-by-5-by-6 arrays]
(array character (3 *)) ;@r[Two-dimensional arrays of characters]
; @r[that have exactly three rows]
(array short-float @empty) ;@r[Zero-rank arrays of short-format]
; @r[floating-point numbers]
@Endlisp
Note that @f[(array t)] is a proper subset of @f[(array *)].
The reason is that @f[(array t)] is the set of arrays that can
hold any @clisp object (the elements are of type @f[t],
which includes all objects). On the other hand, @f[(array *)]
is the set of all arrays whatsoever, including for example
arrays that can hold only characters. Now
@f[(array character)] is not a subset of @f[(array t)]; the two sets
are in fact disjoint because @f[(array character)] is not the
set of all arrays that can hold characters, but rather the set of
arrays that are specialized to hold precisely characters and no
other objects. To test whether an array @f[foo] can hold a character,
one should not use
@lisp
(typep foo '(array character))
@endlisp
but rather
@lisp
(subtypep 'character (array-element-type foo))
@endlisp
See @Funref[array-element-type].
@End[Multiple]
@Begin[Multiple, need 2]
@f[(simple-array @i[element-type] @i[dimensions])]@\This is equivalent
to @f[(array @i[element-type] @i[dimensions])] except that it additionally
specifies that objects of the type are @i[simple] arrays.
(See section @ref[ARRAY-TYPE-SECTION].)
@End[Multiple]
@Begin[Multiple, need 2]
@f[(vector @i[element-type] @i[size])]@\This denotes the set of specialized
one-dimensional arrays whose elements are all of type @i[element-type]
and whose lengths match @i[size]. This is entirely equivalent to
@f[(array @i[element-type] (@i[size]))].
For example:
@lisp
(vector double-float) ;@r[Vectors of double-format]
; @r[floating-point numbers]
(vector * 5) ;@r[Vectors of length 5]
(vector t 5) ;@r[General vectors of length 5]
(vector (mod 32) *) ;@r[Vectors of integers between 0 and 31]
@Endlisp
The specialized types @f[(vector string-char)] and @f[(vector bit)] are so
useful that they have the special names @f[string] and @f[bit-vector].
Every implementation of @clisp must provide distinct representations for
these as distinct specialized data types.
@End[Multiple]
@Begin[Multiple, need 2]
@f[(simple-vector @i[size])]@\This is the same
as @f[(vector t @i[size])] except that it additionally specifies
that its elements are @i[simple] general vectors.
@End[Multiple]
@Begin[Multiple, need 2]
@f[(complex @i[type])]@\Every element of this type is a
complex number whose real part
and imaginary part are each of type @i[type].
For declaration purposes, this type encompasses those complex numbers
that can result by giving numbers of the specified type
to the function @Funref[complex]; this may be different
from what the type means for discrimination purposes.
As an example, Gaussian integers might be
described as @f[(complex integer)], even in implementations
where giving two integers to the function @f[complex] results
in an object of type @f[(complex rational)].
@End[Multiple]
@Begin[Multiple, need 2]
@f[(function (@i[arg1-type] @i[arg2-type] ...) @i[value-type])]@\@}
This type may be used only for declaration and not for discrimination;
@Funref[typep] will signal an error if it encounters a specifier of this form.
Every element of this type is
a function that accepts arguments at @i[least] of the
types specified by the @i[argj-type] forms and returns a value that is a
member of the types specified by the @i[value-type] form. The
@optional, @rest, and @key markers may appear in the list of argument types.
The @i[value-type] may be a @f[values] type specifier in order to indicate the
types of multiple values.
As an example, the function @Funref[cons] is of type @f[(function (t t) cons)],
because it can accept any two arguments and always returns a cons.
The function @f[cons] is
also of type @f[(function (float string) list)], because it can certainly
accept a floating-point number and a string (among other things), and its
result is always of type @f[list] (in fact a @f[cons] is never @f[null],
but that does not matter for this type declaration).
The function @Funref[truncate] is of type @f[(function (number number) (values number number))], as well as of type
@f[(function (integer (mod 8)) integer)].
@End[Multiple]
@Begin[Multiple, need 2]
@f[(values @i[value1-type] @i[value2-type] ...)]@\@}
This type specifer is extremely restricted: it may be used @i[only]
as the @i[value-type] in a @f[function] type specifier or in
a @Specref[the] special form. It is used to specify individual types when
multiple values are involved.
The
@optional, @rest, and @key markers may appear in the @i[value-type] list;
they thereby indicate the parameter list of a
function that, when given to @Specref[multiple-value-call] along with
the values, would be suitable for receiving those values.
@End[Multiple]
@End[Description]
@Section[Type Specifiers that Abbreviate]
The following type specifiers are, for the most part,
abbreviations for other type specifiers that would be far too
verbose to write out explicitly (using, for example, @f[member]).
@Begin[Description]
@Begin[Multiple, need 2]
@f[(integer @i[low] @i[high])]@\Denotes the integers between
@i[low] and @i[high]. The limits @i[low] and @i[high]
must each be an integer, a list of an integer, or unspecified.
An integer is an inclusive limit,
a list of an integer is an exclusive limit, and
@f[*] means that a limit does not exist
and so effectively denotes minus or plus infinity, respectively.
The type @f[fixnum] is simply a name
for @f[(integer @i[smallest] @i[largest])] for implementation-dependent
values of @i[smallest] and @i[largest]
(see @Conref[most-negative-fixnum] and @conref[most-positive-fixnum]).
The type @f[(integer 0 1)]
is so useful that it has the special name @f[bit].
@End[Multiple]
@f[(mod @i[n])]@\Denotes the set of non-negative integers less than @i[n].
This is equivalent to @f[(integer 0 @i[n@minussign@;1])]
or to @f[(integer 0 (@i[n]))].
@Begin[Multiple, need 2]
@f[(signed-byte @i[s])]@\Denotes the set of integers that can be represented
in two's-complement form in a byte of @i[s] bits. This is
equivalent to
@f[(integer @r[@Minussign@;2@+[@superi[s]@superMinussign@;1]] @r[2@+[@superi[s]@superminussign@;1]@Minussign@;1])].
Simply @f[signed-byte] or @f[(signed-byte *)] is the same as @f[integer].
@End[Multiple]
@Begin[Multiple, need 2]
@f[(unsigned-byte @i[s])]@\Denotes the set of non-negative integers that can be
represented in a byte of @i[s] bits. This is equivalent to @f[(mod
@r[2@+[@superi[s]]])], that is, @f[(integer 0 @r[2@+[@superi[s]]@superMinussign@;1])].
Simply @f[unsigned-byte] or @f[(unsigned-byte *)] is the same as
@f[(integer 0 *)], the set of non-negative integers.
@End[Multiple]
@Begin[Multiple, need 2]
@f[(rational @i[low] @i[high])]@\Denotes the rationals between
@i[low] and @i[high]. The limits @i[low] and @i[high]
must each be a rational, a list of a rational, or unspecified.
A rational is an inclusive limit,
a list of a rational is an exclusive limit, and
@f[*] means that a limit does not exist
and so effectively denotes minus or plus infinity, respectively.
@End[Multiple]
@Begin[Multiple, need 2]
@f[(float @i[low] @i[high])]@\Denotes the set of floating-point numbers between
@i[low] and @i[high]. The limits @i[low] and @i[high]
must each be a floating-point number, a list of a floating-point number,
or unspecified; a floating-point number is an inclusive limit, a list of a
floating-point number is an exclusive limit, and
@f[*] means that a limit does not exist
and so effectively denotes minus or plus infinity, respectively.
In a similar manner, one may use:
@Lisp
(short-float@ @i[low]@ @i[high])
(single-float@ @i[low]@ @i[high])
(double-float@ @i[low]@ @i[high])
(long-float@ @i[low]@ @i[high])
@Endlisp
In this case, if a limit is a floating-point
number (or a list of one), it must be one of the appropriate format.
@End[Multiple]
@Begin[Multiple, need 2]
@f[(string @i[size])]@\Means the same as
@f[(array string-char (@i[size]))]: the set of strings of the indicated size.
@End[Multiple]
@Begin[Multiple, need 2]
@f[(simple-string @i[size])]@\Means the same
as @f[(simple-array string-char (@i[size]))]: the set of simple
strings of the indicated size.
@End[Multiple]
@Begin[Multiple, need 2]
@f[(bit-vector @i[size])]@\Means the same as @f[(array bit (@i[size]))]:
the set of bit-vectors of the indicated size.
@End[Multiple]
@Begin[Multiple, need 2]
@f[(simple-bit-vector @i[size])]@\This means the same as
@f[(simple-array bit (@i[size]))]: the set of bit-vectors of
the indicated size.
@End[Multiple]
@End[Description]
@Section[Defining New Type Specifiers]
New type specifiers can come into existence in two ways.
First, defining a new structure type with @Macref[defstruct] automatically
causes the name of the structure to be a new type specifier symbol.
Second, the @f[deftype] special form can be used to define new type-specifier
abbreviations.
@Defmac[Fun {deftype⎇, Args {@i[name] @i[lambda-list] @Mstar<@i[declaration] @mor @i[doc-string]> @Mstar<@i[form]>⎇]
This is very similar to a @Macref[defmacro] form: @i[name] is the
symbol that identifies the type specifier being defined, @i[lambda-list] is
a lambda-list (and may contain @optional and @rest
markers), and
the @i[forms] constitute the body of the expander function. If we view a
type specifier list as a list containing the type specifier name and some argument forms,
the argument forms (unevaluated) are bound to the corresponding
parameters in @i[lambda-list]. Then the body forms are evaluated
as an implicit @f[progn], and the value of the last form
is interpreted as a new type specifier for which the original specifier
was an abbreviation. The @i[name] is returned as the value of the
@f[deftype] form.
@f[deftype] differs from @f[defmacro] in that if no @i[initform]
is specified for an @optional parameter, the default value
is @f[*], not @nil.
If the optional documentation string @i[doc-string] is present,
then it is attached to the @i[name]
as a documentation string of type @f[type]; see @Funref[documentation].
Here are some examples of the use of @f[deftype]:
@lisp
(deftype mod (n) @bq@;(integer 0 (,n)))
(deftype list () '(or null cons))
(deftype square-matrix (@optional type size)
"SQUARE-MATRIX includes all square two-dimensional arrays."
@bq@;(array ,type (,size ,size)))
(square-matrix short-float 7) @r[means] (array short-float (7 7))
(square-matrix bit) @r[means] (array bit (* *))
@Endlisp
If the type name defined by @f[deftype] is used simply as a type
specifier symbol, it is interpreted as a type specifier list with
no argument forms. Thus, in the example above, @f[square-matrix]
would mean @f[(array * (* *))], the set of two-dimensional arrays.
This would unfortunately fail to convey the constraint that the two
dimensions be the same; @f[(square-matrix bit)] has the same problem.
A better definition is:
@Lisp
(defun equidimensional (a)
(or (< (array-rank a) 2)
(apply #'= (array-dimensions a))))
(deftype square-matrix (@optional type size)
@bq@;(and (array ,type (,size ,size))
(satisfies equidimensional)))
@Endlisp
@Enddefmac
@Section[Type Conversion Function]
The following function may be used to convert an object to an
equivalent object of another type.
@Defun[Fun {coerce⎇, Args {@i[object] @i[result-type]⎇]
The @i[result-type] must be a type specifier; the @i[object] is converted
to an ``equivalent'' object of the specified type.
If the coercion cannot be performed, then an error is signalled.
In particular, @f[(coerce x 'nil)] always signals an error.
If @i[object] is already of the specified type, as determined
by @Funref[typep], then it is simply returned.
It is not generally
possible to convert any object to be of any type whatsoever; only certain
conversions are permitted:
@Begin[Itemize]
@Begin[Multiple]
Any sequence type may be converted to any other sequence type, provided
the new sequence can contain all actual elements of the old sequence
(it is an error if it cannot). If the @i[result-type] is specified as
simply @f[array], for example, then @f[(array t)] is assumed. A
specialized type such as @f[string] or @f[(vector (complex short-float))]
may be specified; of course, the result may be of either that type or
some more general type, as determined by the implementation.
Elements of the new sequence will be @f[eql] to corresponding elements
of the old sequence.
If the
@i[sequence] is already of the specified type, it may be returned without
copying it; in this, @f[(coerce @i[sequence] @i[type])] differs from
@f[(concatenate @i[type] @i[sequence])], for the latter is required to
copy the argument @i[sequence]. In particular, if one specifies
@f[sequence], then the argument may simply be returned if it already is
a @f[sequence].
@Lisp
(coerce '(a b c) 'vector) @EV #(a b c)
@Endlisp
@End[Multiple]
@Begin[Multiple]
Some strings, symbols, and integers may be converted to characters.
If @i[object] is a string of length 1, then the
sole element of the string is returned. If @i[object] is a symbol
whose print name is of length 1, then the sole element of the print name
is returned. If @i[object] is an integer @i[n], then @f[(int-char @i[n])]
is returned. See @Funref[character].
@Lisp
(coerce "a" 'character) @EV #\a
@Endlisp
@End[Multiple]
@Begin[Multiple]
Any non-complex number can be converted to a @f[short-float],
@f[single-float], @f[double-float], or @f[long-float]. If simply @f[float]
is specified, and @i[object] is not already a @f[float] of some kind, then
the object is converted to a @f[single-float].
@Lisp
(coerce 0 'short-float) @EV 0.0S0
(coerce 3.5L0 'float) @EV 3.5L0
(coerce 7/2 'float) @EV 3.5
@Endlisp
@End[Multiple]
@Begin[Multiple]
Any number can be converted to a complex number.
If the number is not already complex, then a zero imaginary part
is provided by coercing the integer zero to the type of the given real part.
(If the given real part is rational, however, then the rule of
canonical representation for complex rationals will result
in the immediate re-conversion of the result from type @f[complex]
back to type @f[rational].)
@Lisp
(coerce 4.5s0 'complex) @EV #C(4.5S0 0.0S0)
(coerce 7/2 'complex) @EV 7/2
(coerce #C(7/2 0) '(complex double-float))
@EV #C(3.5D0 0.0D0)
@Endlisp
@End[Multiple]
@Begin[Multiple]
Any object may be coerced to type @f[t].
@lisp
(coerce x 't) @EQ (identity x) @EQ x
@endlisp
@End[Multiple]
@End[Itemize]
Coercions from floating-point numbers to rationals and from ratios
to integers are purposely @i[not] provided because of rounding
problems. The functions @Funref[rational], @f[rationalize],
@Funref[floor], @f[ceiling], @f[truncate], and @f[round] may be used for
such purposes. Similarly, coercions from characters to integers
are purposely not provided; @Funref[char-code] or @Funref[char-int] may be
used explicitly to perform such conversions.
@Enddefun
@Section[Determining the Type of an Object]
The following function may be used to obtain a type specifier
describing the type of a given object.
@Defun[Fun {type-of⎇, Args {@i[object]⎇]
@f[(type-of @i[object])] returns an implementation-dependent result:
some @i[type] of which the @i[object] is a member. Implementors
are encouraged to arrange for
@f[type-of] to return the most specific type that can be
conveniently computed and is likely to be useful to the user.
If the argument is a user-defined named
structure created by @f[defstruct], then @f[type-of] will return the type name
of that structure.
Because the result is implementation-dependent, it is usually better
to use @f[type-of] primarily for debugging purposes;
however, in a few situations portable code requires the use of
@f[type-of], such as when the result is to be given to the
@Funref[coerce] or @Funref[map] function.
On the other hand, often the @Funref[typep] function
or the @Macref[typecase] construct
is more appropriate than @f[type-of].
@Incompatibility{In @maclisp the function @f[type-of] is called @f[typep],
and anomalously so, for it is not a predicate.⎇
@Enddefun